ShiftMeteoWithLapse Subroutine

public subroutine ShiftMeteoWithLapse(input, lapse, refelev, output, dt)

shift meteo observations to reference elevation applying lapse rate

Arguments

Type IntentOptional Attributes Name
type(ObservationalNetwork), intent(in) :: input

actual station network

type(grid_real), intent(in) :: lapse

lapse rate grid

real(kind=float), intent(in) :: refelev

reference elevation

type(ObservationalNetwork), intent(inout) :: output

station network at reference elevation

integer, intent(in), optional :: dt

used when lapse rate is a flux


Variables

Type Visibility Attributes Name Initial
integer, public :: c
logical, public :: check
real(kind=float), public :: deltat
integer, public :: i
integer, public :: j
integer, public :: r
real(kind=float), public :: x
real(kind=float), public :: y

Source Code

SUBROUTINE ShiftMeteoWithLapse &
!
(input, lapse, refelev, output, dt)

IMPLICIT NONE

!Arguments with intent(in):
TYPE (ObservationalNetwork), INTENT(IN) :: input  !!actual station network
TYPE (grid_real), INTENT(IN) :: lapse  !! lapse rate grid
REAL (KIND = float), INTENT(IN) :: refelev !!reference elevation
INTEGER, OPTIONAL, INTENT(IN) :: dt !! used when lapse rate is a flux

!Arguments with intent(inout):
TYPE (ObservationalNetwork), INTENT(INOUT) :: output !!station network at reference elevation

!local eclarations:
INTEGER :: i, j, r, c
REAL (KIND = float) :: x, y
LOGICAL            :: check
REAL (KIND = float) :: deltat

!------------end of declaration------------------------------------------------

IF (PRESENT (dt)) THEN
   deltat = dt
ELSE
   deltat = 1.
END IF

!dato al livello di riferimento
	DO i = 1, input % countObs
		IF (input % obs(i) % value == input % nodata) THEN
			output % obs(i) % value = output % nodata
		ELSE
		    x = input % obs(i) % xyz % easting
		    y = input % obs(i) % xyz % northing
	        CALL GetIJ (x, y, lapse, r, c, check)
	        IF (check) THEN ! lapse rate is defined at location x,y
	            IF (lapse % mat (r,c) /= lapse % nodata) THEN 
			              output % obs(i) % value = input % obs(i) % value + &
                          (refelev - input % obs(i) % xyz % elevation) * &
                           lapse % mat(r,c) * deltat
			        ELSE
			            output % obs(i) % value = input % obs(i) % value
			        END IF
			    ELSE
			        output % obs(i) % value = input % obs(i) % value
			END IF
		END IF
	END DO


RETURN
END SUBROUTINE ShiftMeteoWithLapse